home *** CD-ROM | disk | FTP | other *** search
- include hobbes.inc
- include extrn.inc
-
-
- .DATA
- ; Plane masks for clipping left and right edges of rectangle.
- LeftClipPlaneMask db 00fh,00eh,00ch,008h
- RightClipPlaneMask db 001h,003h,007h,00fh
-
- .CODE
- ;--------------------------------------------------------------------------
- ; void HLine( int X1, int X2, int Y, char COLOR )
- ; void HLineClip( int X1, int X2, int Y, char COLOR )
- ;
-
- public _HLineClip
- _HLineClip proc
- ARG X1:WORD, X2:WORD, Y:WORD, COLOR:WORD
- push bp
- mov bp,sp
- push ds
- mov ax,@data
- mov ds,ax
-
- mov ax,Y
- cmp ax,_ClipTop
- jl @@hlc_exit
- cmp ax,_ClipBottom
- jg @@hlc_exit
- mov ax,X1
- cmp ax,_ClipRight
- jg @@hlc_exit
- cmp ax,_ClipLeft
- jge @@hlc_1
- mov ax,_ClipLeft
- mov X1,ax
- @@hlc_1:
- mov ax,X2
- cmp ax,_ClipLeft
- jl @@hlc_exit
- cmp ax,_ClipRight
- jle hlc_2
- mov ax,_ClipRight
- mov X2,ax
- jmp short hlc_2
- @@hlc_exit:
- pop ds
- pop bp
- ret
- _HLineClip endp
-
- public _HLine
- _HLine proc far
- push bp
- mov bp,sp
- push ds
- mov ax,@data
- mov ds,ax
- hlc_2:
- mov es,_ModeX_Segment ; point ES:DI to the left pixel's address
- push si
- push di
-
- cld
- mov di,Y
- shl di,1
- mov di,word ptr _RowOffset[di]
- mov ax,X1
- shr ax,2 ; X/4 = offset of pixel in scan line
- add di,ax ; final offset of pixel in page
- add di,_Display_Offset
-
- mov dx,SC_INDEX ; set the Sequence Controller Index to
- mov al,MAP_MASK ; point to the Map Mask register
- out dx,al
- inc dx ; point DX to the SC Data register
-
- mov si,X1
- and si,0003h ; look up left edge plane mask
- mov bh,LeftClipPlaneMask[si] ; to clip & put in BH
- mov si,X2
- and si,0003h ; look up right edge plane
- mov bl,RightClipPlaneMask[si] ; mask to clip & put in BL
-
- mov cx,X2 ; calculate # of addresses across line
- mov si,X1
- and si,not 011b
- sub cx,si
- shr cx,2 ; # of addresses across line to draw - 1
- jnz @@HL_MasksSet ; there's more than one byte to draw
- and bh,bl ; there's only one byte, so combine the left
- ; and right edge clip masks
- @@HL_MasksSet:
- mov ah,byte ptr COLOR
- mov al,bh ; put left-edge clip mask in AL
- out dx,al ; set the left-edge plane (clip) mask
- mov al,ah ; put color in AL
- stosb ; draw the left edge
- dec cx ; count off left edge byte
- js @@HL_Done ; that's the only byte
- jz @@HL_DoRtEdge ; there are only two bytes
- mov al,00fh ; middle addresses are drawn 4 pixels at a pop
- out dx,al ; set the middle pixel mask to no clip
- mov al,ah ; put color in AL
- shr cx,1
- rep stosw ; draw the middle addresses four pixels apiece
- adc cx,0
- rep stosb
- @@HL_DoRtEdge:
- mov al,bl ; put right-edge clip mask in AL
- out dx,al ; set the right-edge plane (clip) mask
- mov al,ah ; put color in AL
- stosb ; draw the right edge
- @@HL_Done:
- pop di ; restore caller's register variables
- pop si
- pop ds
- pop bp ; restore caller's stack frame
- ret
- _HLine endp
-
-
-
-
- ;-----------------------------------------------------------------------
- ; void VLine( int X, int Y1, int Y2, char COLOR )
- ; void VLineClip( int X, int Y1, int Y2, char COLOR )
- ;
- public _VLineClip
- _VLineClip proc
- ARG X:WORD, Y1:WORD, Y2:WORD, COLOR:WORD
- push bp
- mov bp,sp
- push ds
- mov ax,@data
- mov ds,ax
-
- mov ax,X
- cmp ax,_ClipLeft
- jl @@vlc_exit
- cmp ax,_ClipRight
- jg @@vlc_exit
- mov ax,Y1
- cmp ax,_ClipBottom
- jg @@vlc_exit
- cmp ax,_ClipTop
- jge @@vlc_1
- mov ax,_ClipTop
- mov Y1,ax
- @@vlc_1:
- mov ax,Y2
- cmp ax,_ClipTop
- jl @@vlc_exit
- cmp ax,_ClipBottom
- jle vlc_2
- mov ax,_ClipRight
- mov Y2,ax
- jmp short vlc_2
- @@vlc_exit:
- pop ds
- pop bp
- ret
- _VLineClip endp
-
- public _VLine
- _VLine proc far
- push bp
- mov bp,sp
- push ds
- mov ax,@data
- mov ds,ax
- vlc_2:
- mov es,_ModeX_Segment ; put video segment in ES
-
- mov cl,byte ptr X ; set the drawing plane for the vline
- and cl,011b ; CL = vline's plane
- mov ax,0100h+MAP_MASK ; AL = index in SC of Map Mask reg
- shl ah,cl ; set only the bit for the vline's plane to 1
- mov dx,SC_INDEX ; set the Map Mask to enable only
- out dx,ax ; the vline's plane
-
- mov bx,Y1 ; compute the starting address of the vline
- shl bx,1
- mov bx,word ptr _RowOffset[bx]
- mov ax,X
- shr ax,2 ; X/4 = offset of pixel in scan line
- add bx,ax ; final offset of pixel in page
- add bx,_Display_Offset ; adjust for current page
-
- mov cx,Y2
- sub cx,Y1 ; compute number of pixels in line - 1
-
- mov al,byte ptr COLOR
- @@vl_loop:
- mov es:[bx],al ; set the current pixel
- add bx,_Virtual_Width_Addr ; jump to the pixel below
- dec cx ; decrement the counter
- jge @@vl_loop ; loop until less than zero
-
- pop ds
- pop bp
- ret
- _VLine endp
-
-
-
-
- ;-----------------------------------------------------------------------
- ; void HLineR( int X1, int X2, int Y, char COLOR )
- ; void HLineClipR( int X1, int X2, int Y, char COLOR )
- ;
- ; Draws a horizontal line from (X1, Y) to (X2, Y).
- ; Uses Watcom Parameter passing convention in registers
- ;
- ; X1 in AX
- ; X2 in DX
- ; Y in CX
- ; Color in BX
-
- public _HLineClipR
- _HLineClipR proc
- push ds
- push @data
- pop ds
-
- cmp cx,_ClipTop
- jl @@hlc_exitR
- cmp cx,_ClipBottom
- jg @@hlc_exitR
-
- cmp ax,_ClipRight
- jg @@hlc_exitR
- cmp ax,_ClipLeft
- jge @@hlc_1R
- mov ax,_ClipLeft
-
- @@hlc_1R:
- cmp dx,_ClipLeft
- jl @@hlc_exitR
- cmp dx,_ClipRight
- jle hlc_2R
- mov dx,_ClipRight
- jmp short hlc_2R
- @@hlc_exitR:
- pop ds
- ret
- _HLineClipR endp
-
-
- public _HLineR
- _HLineR proc far
- push ds
- push @data
- pop ds
- hlc_2R:
- mov es,_ModeX_Segment ; point ES:DI to the left pixel's address
- push si
- push di
-
- cld
- mov di,cx
- shl di,1
- mov di,word ptr _RowOffset[di]
- mov si,ax
- shr si,2 ; X/4 = offset of pixel in scan line
- add di,si ; final offset of pixel in page
- add di,_Display_Offset ; adjust for current page
-
- mov cx,bx
- mov si,ax
- and si,0003h ; look up left edge plane mask
- mov bh,LeftClipPlaneMask[si] ; to clip & put in BH
- mov si,dx
- and si,0003h ; look up right edge plane
- mov bl,RightClipPlaneMask[si] ; mask to clip & put in BL
-
- mov si,ax
- mov ah,cl ; Get the Color for later
- mov cx,dx ; calculate # of addresses across line
- ; DI-~Y,SI-X1,AH-C,CX-X2,BX-mask
- ; AL,DX
-
- mov dx,SC_INDEX ; set the Sequence Controller Index to
- mov al,MAP_MASK ; point to the Map Mask register
- out dx,al
- inc dx ; point DX to the SC Data register
-
- and si,not 011b
- sub cx,si
- shr cx,2 ; # of addresses across line to draw - 1
- jnz @@HL_MasksSetR ; there's more than one byte to draw
- and bh,bl ; there's only one byte, so combine the left
- ; and right edge clip masks
- @@HL_MasksSetR:
- mov al,bh ; put left-edge clip mask in AL
- out dx,al ; set the left-edge plane (clip) mask
- mov al,ah ; put color in AL
- stosb ; draw the left edge
- dec cx ; count off left edge byte
- js @@HL_DoneR ; that's the only byte
- jz @@HL_DoRtEdgeR ; there are only two bytes
- mov al,00fh ; middle addresses are drawn 4 pixels at a pop
- out dx,al ; set the middle pixel mask to no clip
- mov al,ah ; put color in AL
- shr cx,1
- rep stosw ; draw the middle addresses four pixels apiece
- adc cx,0
- rep stosb
- @@HL_DoRtEdgeR:
- mov al,bl ; put right-edge clip mask in AL
- out dx,al ; set the right-edge plane (clip) mask
- mov al,ah ; put color in AL
- stosb ; draw the right edge
- @@HL_DoneR:
- pop di
- pop si
- pop ds
- ret
- _HLineR endp
-
-
-
-
- ;-----------------------------------------------------------------------
- ; void Line( int X1, int Y1, int X2, int Y2, int COLOR )
-
-
- public _Line
- _Line proc
- ARG X1:WORD, Y1:WORD, X2:WORD, Y2:WORD, COLOR:WORD
- push bp
- mov bp,sp
- push ds
-
- mov ax,@data
- mov ds,ax
-
- mov es,_ModeX_Segment
- push si
- push di
-
- mov ax,_Virtual_Width_Addr
- mov byte ptr cs:mod_3+2,al
- mov byte ptr cs:mod_6+2,al
-
- mov ax,X1
- sub ax,X2 ; compute ax=DX=|X1-X2|
- jge short line_1
- neg ax
- line_1:
- mov si,Y1
- sub si,Y2 ; compute si=DY=|Y1-Y2|
- jge short line_2
- neg si
- line_2:
- cmp si,ax
- jle line_small_slope
- jmp line_big_slope
-
- line_small_slope: ; DX>=DY
- mov cx,si ; cx=DY
- shl si,1 ; si=2DY
- mov cs:(mod_1-2),si ; CONST1=2DY>=0 (need segment override?)
- sub cx,ax ; cx=DY-DX
- shl cx,1 ; cx=2(DY-DX)
- mov cs:(mod_2-2),cx ; CONST2=2(DY-DX)<=0
- sub si,ax ; parameter si=P=2DY-DX
-
- mov di,X1 ; these should probably go at the top where
- mov bx,X2 ; X1,X2 are first loaded from the stack
- cmp di,bx
- jl short line_3 ;
- mov di,bx ; X1>X2, so di has starting x value (X2)
- mov bx,Y2 ; bx has starting y value (Y2)
- cmp bx,Y1
- jl line_2_add_y
- mov word ptr cs:mod_3,0EF83h ; Hex for sub di,(immediate)
- jmp short line_2_3_again
- line_2_add_y:
- mov word ptr cs:mod_3,0C783h ; Hex for add di,(immediate)
- jmp short line_2_3_again
- line_3: ; X1<X2, so di has starting x value (X1)
- mov bx,Y1 ; bx has starting y value (Y1)
- cmp bx,Y2
- jl line_3_add_y
- mov word ptr cs:mod_3,0EF83h ; Hex for sub di,(immediate)
- jmp short line_2_3_again
- line_3_add_y:
- mov word ptr cs:mod_3,0C783h ; Hex for add di,(immediate)
- line_2_3_again:
- shl bx,1 ; index into big RowOffset table to get
- mov bx,word ptr _RowOffset[bx] ; scan line address
- mov cx,di ; save X for computation of MapMask
- shr di,2 ; add offset (X/4) of pixel in scan line
- add di,bx ; and store in di
- mov bx,ax ; save count DX
-
- ; Our story so far:
- ; si = P
- ; bx = DX
- ; ax = DX
- ; cx = min(X1,X2)
- ; di = pixel address
- ; dx = ?
-
- and cl,011b ; cl = pixel's plane
- mov ax,1100h+MAP_MASK ; al = index in SC of Map Mask reg
- shl ah,cl ; set only the bit for the pixel's plane to 1
-
- mov cx,bx ; restore count to cx
- mov dx,SC_INDEX ; set the Map Mask to enable only
- ; the pixel's plane
- mov bl,byte ptr COLOR
- jmp short line_set_pixel
-
- line_loop1:
- rol ah,1 ; next x
- adc di,0
- cmp si,0
- jge line_neg_p1
-
- add si,2112h ; next p
- ; SELF-MODIFYING (replace 0000 with CONST1)
- mod_1 label word ; label for modification
-
- jmp short line_set_pixel
- mod_3 label word
- line_neg_p1:
- add di,80 ; next y (add or subtract row width)
- ; SELF-MODIFYING (add/sub)
-
- add si,4269h ; next p
- ; SELF-MODIFYING (replace 0000 with CONST2)
- mod_2 label word ; label for modification
-
- line_set_pixel:
- out dx,ax
- mov es:[di],bl ; set the pixel (no segment override?)
- dec cx
- jge line_loop1
-
- jmp line_done
-
-
- line_big_slope: ; DY>DX
- mov bx,ax ; bx=DX
- shl ax,1 ; ax=2DX
- mov cs:(mod_4-2),ax ; CONST1=2DX>=0
- mov dx,si ; dx=DY
- shl si,1 ; si=2DY
- sub ax,si ; ax=2(DX-DY)
- mov cs:(mod_5-2),ax ; CONST2=2(DX-DY)<=0
- mov si,ax ; si=2DX-2DY
- add si,dx ; si=P=2DX-DY
-
- mov di,X1 ; these should probably go at the top where
- mov bx,X2 ; X1,X2 are first loaded from the stack
- cmp di,bx
- jl short line_6 ;
- mov di,bx ; X1>=X2, so di has starting x value (X2)
- mov bx,Y2 ; bx has starting y value (Y2)
- cmp bx,Y1
- jl line_5_add_y
- mov word ptr cs:mod_6,0EF83h ; Hex for sub di,(immediate)
- jmp short line_5_6_again
- line_5_add_y:
- mov word ptr cs:mod_6,0C783h ; Hex for add di,(immediate)
- jmp short line_5_6_again
- line_6: ; X1<X2, so di has starting x value (X1)
- mov bx,Y1 ; bx has starting y value (Y1)
- cmp bx,Y2
- jl line_6_add_y
- mov word ptr cs:mod_6,0EF83h ; Hex for sub di,(immediate)
- jmp short line_5_6_again
- line_6_add_y:
- mov word ptr cs:mod_6,0C783h ; Hex for add di,(immediate)
- line_5_6_again:
- shl bx,1 ; index into big RowOffset table to get
- mov bx,word ptr _RowOffset[bx] ; scan line address
- mov cx,di ; save X for computation of MapMask
- shr di,2 ; add offset (X/4) of pixel in scan line
- add di,bx ; and store in di
-
- ; Our story so far:
- ; si = P
- ; bx = address
- ; ax = CONST2
- ; cx = DY
- ; di = pixel address
- ; dx = DY
-
- and cl,011b ; cl = pixel's plane
- mov ax,1100h+MAP_MASK ; al = index in SC of Map Mask reg
- shl ah,cl ; set only the bit for the pixel's plane to 1
-
- mov cx,dx ; restore count to cx
-
- mov bl,byte ptr COLOR
- mov dx,SC_INDEX ; set the Map Mask to enable only
- ; the pixel's plane
- jmp short line_loop_enter_2
-
- mod_6 label word
- line_loop2:
- add di,80 ; next y (add or subtract row width)
- ; SELF-MODIFYING (add/sub)
- cmp si,0
- jge line_neg_p2
- add si,2001 ; next p
- ; SELF-MODIFYING (replace 0000 with CONST1)
- mod_4 label word ; label for modification
- jmp short line_set_pixel2
- line_neg_p2:
- rol ah,1 ; next x
- adc di,0
- add si,0Bach ; next p
- ; SELF-MODIFYING (replace 0000 with CONST2)
- mod_5 label word ; label for modification
- line_loop_enter_2:
- out dx,ax
- line_set_pixel2:
- mov es:[di],bl ; set the pixel
- dec cx
- jge line_loop2
-
- line_done:
- pop di ; restore caller's register variables
- pop si
- pop ds
- pop bp ; restore caller's stack frame
- ret
- _Line endp
-
-
-
- ;----------------------------------------------------------------------------
- END